ReadSoilTypes Subroutine

private subroutine ReadSoilTypes(inifile)

read soil types from external file

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inifile

stores configuration information


Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: i
integer(kind=short), public :: nsoils
type(IniList), public :: soilDB

Source Code

SUBROUTINE ReadSoilTypes   & 
  !
  (inifile)           

IMPLICIT NONE

!Arguments with intent(in):
CHARACTER (LEN = *), INTENT(IN) :: inifile !!stores configuration information

!local declarations
TYPE(IniList) :: soilDB
INTEGER (KIND = short) :: nsoils !number of soil types to read
INTEGER (KIND = short) :: i

!------------end of declaration------------------------------------------------ 

!open and read soil types file
CALL IniOpen (inifile, soilDB)

!get number of soil types to read
IF (KeyIsPresent ('soil-types', soilDB) ) THEN !mandatory key
   nsoils = IniReadInt ('soil-types', soilDB)
ELSE
    CALL Catch ('error', 'SoilBalance', &
       'missing ''soil-types'' section in soil types file') 
END IF

!allocate memory and read data
ALLOCATE (soils(nsoils))
DO i = 1, nsoils
  soils (i) % ksat = IniReadDouble ('ksat', soilDB, section = ToString(i)) 
  soils (i) % thetas = IniReadDouble ('thetas', soilDB, section = ToString(i)) 
  soils (i) % thetar = IniReadDouble ('thetar', soilDB, section = ToString(i))
  soils (i) % wp = IniReadDouble ('wp', soilDB, section = ToString(i))
  soils (i) % fc = IniReadDouble ('fc', soilDB, section = ToString(i))
  soils (i) % psic = IniReadDouble ('psic', soilDB, section = ToString(i))
  soils (i) % psdi = IniReadDouble ('psdi', soilDB, section = ToString(i))
  soils (i) % phy = IniReadDouble ('phy', soilDB, section = ToString(i))
  soils (i) % smax = IniReadDouble ('smax', soilDB, section = ToString(i))
  soils (i) % m = IniReadDouble ('m', soilDB, section = ToString(i))
  soils (i) % n = IniReadDouble ('n', soilDB, section = ToString(i))
  soils (i) % pp = IniReadDouble ('p', soilDB, section = ToString(i))
  soils (i) % kx = IniReadDouble ('ksat-matrix', soilDB, section = ToString(i))
  soils (i) % c = IniReadDouble ('c', soilDB, section = ToString(i))
  soils (i) % s0 = IniReadDouble ('s0', soilDB, section = ToString(i))
  soils (i) % cn = IniReadDouble ('cn', soilDB, section = ToString(i))
  
END DO

!deallocate soilDB
CALL IniClose (soilDB)

RETURN
END SUBROUTINE ReadSoilTypes